Initialization of spatial average of meteorological variables
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | fileini | |||
character(len=*), | intent(in) | :: | pathout | |||
type(grid_real), | intent(in) | :: | temp |
air temperarure (°C) |
||
type(grid_real), | intent(in) | :: | tmean |
air temperarure daily mean(°C) |
||
type(grid_real), | intent(in) | :: | tmax |
air temperarure daily max (°C) |
||
type(grid_real), | intent(in) | :: | tmin |
air temperarure daily min (°C) |
||
type(grid_real), | intent(in) | :: | precipitation |
precipitation rate (m/s) |
||
type(grid_real), | intent(in) | :: | rh |
air relative humidity (0-100) |
||
type(grid_real), | intent(in) | :: | radiation |
solar radiation (w/m2) |
||
type(grid_real), | intent(in) | :: | netradiation |
net radiation (w/m2) |
||
type(grid_real), | intent(in) | :: | windspeed |
wind speed (m/s) |
||
type(grid_real), | intent(in) | :: | daily_precipitation |
daily precipitation rate (m/s) |
||
type(grid_real), | intent(in) | :: | irrigation |
irrigation rate (m/s) |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
type(IniList), | public | :: | iniDB |
SUBROUTINE InitSpatialAverageMeteo & ! (fileini, pathout, temp, tmean, tmax, tmin, precipitation, & rh, radiation, netradiation, windspeed, daily_precipitation, & irrigation ) IMPLICIT NONE !arguments with intent in: CHARACTER(LEN = *), INTENT(IN) :: fileini CHARACTER(LEN = *), INTENT(IN) :: pathout TYPE (grid_real), INTENT(IN) :: temp !!air temperarure (°C) TYPE (grid_real), INTENT(IN) :: tmean !!air temperarure daily mean(°C) TYPE (grid_real), INTENT(IN) :: tmax !!air temperarure daily max (°C) TYPE (grid_real), INTENT(IN) :: tmin !!air temperarure daily min (°C) TYPE (grid_real), INTENT(IN) :: precipitation !!precipitation rate (m/s) TYPE (grid_real), INTENT(IN) :: rh !!air relative humidity (0-100) TYPE (grid_real), INTENT(IN) :: radiation !!solar radiation (w/m2) TYPE (grid_real), INTENT(IN) :: netradiation !!net radiation (w/m2) TYPE (grid_real), INTENT(IN) :: windspeed !!wind speed (m/s) TYPE (grid_real), INTENT(IN) :: daily_precipitation !!daily precipitation rate (m/s) TYPE (grid_real), INTENT(IN) :: irrigation !!irrigation rate (m/s) !local declarations TYPE(IniList) :: iniDB !-------------------------------end of declaration----------------------------- ! open and read configuration file CALL IniOpen (fileini, iniDB) ! search for active variable for output CALL Catch ('info', 'SpatialAverage', 'checking for meteo active variables ') countmeteo = 0 !precipitation IF ( IniReadInt ('precipitation', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (precipitation % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'precipitation not allocated, & forced to not export spatial average ') meteoout (1) = .FALSE. ELSE meteoout (1) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (1) = .FALSE. END IF !daily precipitation IF ( IniReadInt ('daily-precipitation', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (daily_precipitation % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'daily precipitation not allocated, & forced to not export spatial average ') meteoout (2) = .FALSE. ELSE meteoout (2) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (2) = .FALSE. END IF !air temperature IF ( IniReadInt ('temperature', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (temp % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'air temperature not allocated, & forced to not export spatial average ') meteoout (3) = .FALSE. ELSE meteoout (3) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (3) = .FALSE. END IF !daily mean air temperature IF ( IniReadInt ('temperature-daily-mean', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (tmean % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'daily mean temperature not allocated, & forced to not export spatial average ') meteoout (4) = .FALSE. ELSE meteoout (4) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (4) = .FALSE. END IF !daily maximum air temperature IF ( IniReadInt ('temperature-daily-max', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (tmax % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'daily maximum temperature not allocated, & forced to not export spatial average ') meteoout (5) = .FALSE. ELSE meteoout (5) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (5) = .FALSE. END IF !daily minimum air temperature IF ( IniReadInt ('temperature-daily-min', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (tmin % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'daily minimum temperature not allocated, & forced to not export spatial average ') meteoout (6) = .FALSE. ELSE meteoout (6) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (6) = .FALSE. END IF !relative humidity IF ( IniReadInt ('relative-humidity', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (rh % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'rh not allocated, & forced to not export spatial average ') meteoout (7) = .FALSE. ELSE meteoout (7) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (7) = .FALSE. END IF ! solar radiation IF ( IniReadInt ('solar-radiation', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (radiation % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'radiation not allocated, & forced to not export spatial average ') meteoout (8) = .FALSE. ELSE meteoout (8) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (8) = .FALSE. END IF ! net radiation IF ( IniReadInt ('net-radiation', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (netradiation % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'net radiation not allocated, & forced to not export spatial average ') meteoout (9) = .FALSE. ELSE meteoout (9) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (9) = .FALSE. END IF !wind speed IF ( IniReadInt ('wind-speed', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (windspeed % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'windspeed not allocated, & forced to not export spatial average ') meteoout (10) = .FALSE. ELSE meteoout (10) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (10) = .FALSE. END IF !irrigation IF ( IniReadInt ('irrigation', iniDB, section = 'meteo') == 1) THEN IF ( .NOT. ALLOCATED (irrigation % mat) ) THEN CALL Catch ('warning', 'SpatialAverage', 'irrigation not allocated, & forced to not export spatial average ') meteoout (11) = .FALSE. ELSE meteoout (11) = .TRUE. countmeteo = countmeteo + 1 END IF ELSE meteoout (11) = .FALSE. END IF meteoInitialized = .TRUE. CALL IniClose (iniDB) CALL ConfigureExtents (fileini, pathout) RETURN END SUBROUTINE InitSpatialAverageMeteo